home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / brklyprl.lha / Emulator / Benchmarks / queens.pl < prev    next >
Encoding:
Text File  |  1989-04-14  |  1.4 KB  |  80 lines

  1.  
  2. /* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
  3.  
  4. %    the queens on a chessboard problem (queens) for 4x4 board
  5.  
  6. main :-  run(4,X), fail.
  7.  
  8. size(4).
  9. int(1).
  10. int(2).
  11. int(3).
  12. int(4).
  13.  
  14. run(Size, Soln) :- get_solutions(Size, Soln), inform(Soln).
  15.  
  16. get_solutions(Board_size, Soln) :- solve(Board_size, [], Soln).
  17.  
  18. %    newsquare generates legal positions for next queen
  19.  
  20. newsquare([], square(1, X)) :- int(X).
  21. newsquare([square(I, J) | Rest], square(X, Y)) :-
  22.     X is I + 1,
  23.     int(Y),
  24.     not(threatened(I, J, X, Y)),
  25.     safe(X, Y, Rest).
  26.  
  27.  
  28. %    safe checks whether square(X, Y) is threatened by any
  29. %    existing queens
  30.  
  31. safe(X, Y, []).
  32. safe(X, Y, [square(I, J) | L]) :-
  33.     not(threatened(I, J, X, Y)),
  34.     safe(X, Y, L).
  35.  
  36.  
  37. %    threatened checks whether squares (I, J) and (X, Y)
  38. %    threaten each other
  39.  
  40. threatened(I, J, X, Y) :-
  41.     (I = X),
  42.     !.
  43. threatened(I, J, X, Y) :-
  44.     (J = Y),
  45.     !.
  46. threatened(I, J, X, Y) :-
  47.     (U is I - J),
  48.     (V is X - Y),
  49.     (U = V),
  50.     !.
  51. threatened(I, J, X, Y) :-
  52.     (U is I + J),
  53.     (V is X + Y),
  54.     (U = V),
  55.     !.
  56.  
  57.  
  58. %    solve accumulates the positions of occupied squares
  59.  
  60. solve(Bs, [square(Bs, Y) | L], [square(Bs, Y) | L]) :- size(Bs).
  61. solve(Board_size, Initial, Final) :-
  62.     newsquare(Initial, Next),
  63.     solve(Board_size, [Next | Initial], Final).
  64.  
  65. inform([]) :- nl,nl.
  66. inform([M | L]) :- write(M), nl, inform(L).
  67.  
  68. %procedure not
  69. %
  70. %    try_me_else    N1
  71. %    allocate
  72. %    escape        call,0
  73. %    cut
  74. %    fail
  75. %
  76. %N1:    trust_me_else    fail
  77. %    proceed
  78.  
  79.  
  80.